home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / smaltalk / gnu_st.lha / gnu_st / smalltalk-1.1.1 / IdentityDictionary.st < prev    next >
Text File  |  1991-09-12  |  8KB  |  297 lines

  1. "======================================================================
  2. |
  3. |   IdentityDictionary Method Definitions
  4. |
  5.  ======================================================================"
  6.  
  7.  
  8. "======================================================================
  9. |
  10. | Copyright (C) 1990, 1991 Free Software Foundation, Inc.
  11. | Written by Steve Byrne.
  12. |
  13. | This file is part of GNU Smalltalk.
  14. |
  15. | GNU Smalltalk is free software; you can redistribute it and/or modify it
  16. | under the terms of the GNU General Public License as published by the Free
  17. | Software Foundation; either version 1, or (at your option) any later version.
  18. | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
  19. | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
  20. | FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
  21. | details.
  22. | You should have received a copy of the GNU General Public License along with
  23. | GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
  24. | Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  
  25. |
  26.  ======================================================================"
  27.  
  28.  
  29. "
  30. |     Change Log
  31. | ============================================================================
  32. | Author       Date       Change 
  33. | sbyrne     25 Apr 89      created.
  34. |
  35. "
  36.  
  37. Dictionary variableSubclass: #IdentityDictionary
  38.        instanceVariableNames: 'values'
  39.        classVariableNames: ''
  40.        poolDictionaries: ''
  41.        category: nil.
  42.  
  43. IdentityDictionary comment:
  44. 'I am similar to dictionary, except that my representation is
  45. different, and I use the object identity comparision message == to
  46. determine equivalence of indices.' !
  47.  
  48. !IdentityDictionary class methodsFor: 'instance creation'!
  49.  
  50. new
  51.     ^self new: 4
  52. !
  53.  
  54. new: anInteger
  55.     ^(super new: anInteger) initValues
  56.  
  57. !!
  58.  
  59.  
  60.  
  61. !IdentityDictionary methodsFor: 'accessing'!
  62.  
  63. add: anAssociation
  64.     self at: anAssociation key put: anAssociation value.
  65.     ^anAssociation
  66. !
  67.  
  68. at: key put: value
  69.     | index |
  70.     index _ self findKeyIndex: key.
  71.     (self basicAt: index) isNil
  72.         ifTrue: [ tally _ tally + 1 ].
  73.     self basicAt: index put: key.
  74.     values basicAt: index put: value.
  75.     ^value
  76. !
  77.  
  78. at: key ifAbsent: aBlock
  79.     | index |
  80.     index _ self findKeyIndex: key.
  81.     (self basicAt: index) isNil
  82.         ifTrue: [ ^aBlock value ].
  83.     ^values basicAt: index
  84. !    
  85.     
  86. associationAt: key ifAbsent: aBlock
  87.     | index assoc|
  88.     ^Association key: key
  89.          value: (self at: key
  90.                       ifAbsent: [ ^aBlock value ])
  91. !
  92.  
  93. keyAtValue: value ifAbsent: exceptionBlock
  94.     self indicesDo:
  95.         [ :i | value = (values basicAt: i)
  96.                  ifTrue: [ ^self basicAt: i] ].
  97.     ^exceptionBlock value
  98. !!
  99.  
  100.  
  101.  
  102. !IdentityDictionary methodsFor: 'dictionary testing'!
  103. includesAssociation: anAssociation
  104.     | index |
  105.     index _ self findKeyIndex: anAssociation key.
  106.     ^(self basicAt: index) notNil
  107.         and: [ (values basicAt: index) = anAssociation value ]
  108. !
  109.  
  110. includesKey: key
  111.     ^(self basicAt: (self findKeyIndex: key)) notNil
  112. !!
  113.  
  114.  
  115.  
  116. !IdentityDictionary methodsFor: 'dictionary removing'!
  117. removeKey: key ifAbsent: aBlock
  118.     | index value|
  119.     index _ self findKeyIndexNoGrow: key ifAbsent: [ ^aBlock value ].
  120.     value _ values basicAt: index.
  121.     self basicAt: index put: nil.
  122.     values basicAt: index put: nil.
  123.     tally _ tally - 1.
  124.     self rehashObjectsAfter: index.
  125.     ^ value
  126. !!
  127.  
  128.  
  129.  
  130. !IdentityDictionary methodsFor: 'dictionary enumerating'!
  131. associationsDo: aBlock
  132.     self indicesDo:
  133.         [ :i | aBlock value: (Association key: (self basicAt: i)
  134.                                       value: (values basicAt: i)) ]
  135. !
  136.  
  137. "These could be implemented more efficiently by 
  138.  doing the explicit scanning of the dictionary by hand"
  139. keysDo: aBlock
  140.     self indicesDo: [ :i | aBlock value: (self basicAt: i) ]
  141. !
  142.  
  143. do: aBlock
  144.     self indicesDo: [ :i | aBlock value: (values basicAt: i) ]
  145. !
  146.  
  147. select: aBlock
  148.     | newDict |
  149.     newDict _ self species new.
  150.     self indicesDo:
  151.         [ :i | (aBlock value: (values basicAt: i))
  152.                  ifTrue: [ newDict add: (Association key: (self basicAt: i)
  153.                                             value: (values basicAt: i))] ].
  154.     ^newDict
  155. !!
  156.  
  157.  
  158.  
  159. !IdentityDictionary methodsFor: 'misc math methods'!
  160.  
  161. = aDictionary
  162.     tally ~= aDictionary size ifTrue: [ ^false ].
  163.     self indicesDo:
  164.         [ :i | (values basicAt: i) = (aDictionary at: (self basicAt: i)
  165.                                               ifAbsent: [ ^false ])
  166.                  ifFalse: [ ^false ] ].
  167.     ^true
  168. !
  169.  
  170. hash
  171.     | hashValue |
  172.     hashValue _ tally.
  173.     self indicesDo:
  174.         [ :i | hashValue _ hashValue + (self basicAt: i) hash.
  175.            hashValue _ hashValue + (values basicAt: i) hash ].
  176.     ^hashValue
  177. !!
  178.  
  179.  
  180.  
  181. !IdentityDictionary methodsFor: 'printing'!
  182.  
  183. printOn: aStream
  184.     aStream nextPutAll: self class name , ' (' .
  185.     aStream nl.
  186.     self indicesDo:
  187.         [ :i | aStream tab.
  188.            (self basicAt: i) storeOn: aStream.
  189.            aStream nextPut: $,.
  190.            (values basicAt: i) storeOn: aStream.
  191.            aStream nl ].
  192.     aStream nextPut: $)
  193. !!
  194.  
  195.  
  196.  
  197. !IdentityDictionary methodsFor: 'storing'!
  198.  
  199. storeOn: aStream
  200.     | hasElements |
  201.     aStream nextPutAll: '(', self class name , ' new'.
  202.     hasElements _ false.
  203.     self indicesDo:
  204.         [ :i | aStream nextPutAll: ' at: '.
  205.                (self basicAt: i) storeOn: aStream.
  206.            aStream nextPutAll: ' put: '.
  207.                (values basicAt: i) storeOn: aStream.
  208.            aStream nextPut: $;.
  209.            hasElements _ true ].
  210.     hasElements ifTrue: [ aStream nextPutAll: ' yourself' ].
  211.     aStream nextPut: $)
  212. !!
  213.  
  214.  
  215.  
  216. !IdentityDictionary methodsFor: 'private methods'!
  217.  
  218. initValues
  219.     values _ Array new: self basicSize
  220. !
  221.  
  222. indicesDo: aBlock
  223.     "Invokes aBlock with all the indices of the set that have valid keys"
  224.     1 to: self basicSize do:
  225.         [ :i | (self basicAt: i) notNil
  226.               ifTrue: [ aBlock value: i ] ]
  227. !    
  228.  
  229. rehashObjectsAfter: index
  230.     "### rehash bug needs to be fixed!!!!"
  231.     "Rehashes all the objects in the collection after index to see if any of
  232.     them hash to index.  If so, that object is copied to index, and the
  233.     process repeats with that object's index, until a nil is encountered."
  234.     | i size count key |
  235.     i _ index.
  236.     size _ self basicSize.
  237.     count _ size.
  238.     [ count > 0 ]
  239.         whileTrue:
  240.         [ i _ i \\ size + 1.
  241.               key _ self basicAt: i.
  242.           key isNil ifTrue: [ ^self ].
  243.               ((key hash \\ size) + 1) = index
  244.               ifTrue: [ self basicAt: index put: key.
  245.                   values basicAt: index put: (values basicAt: i).
  246.                   self basicAt: i put: nil.  "Be tidy"
  247.               values basicAt: i put: nil."Be tidy"
  248.               index _ i ].
  249.               count _ count - 1 ]
  250. !
  251.  
  252. findKeyIndex: aKey ifFull: aBlock
  253.     "Tries to see if aKey exists as the key of an indexed variable (which is an
  254.     association).  If it's searched the entire dictionary and the key is 
  255.     not to be found, aBlock is evaluated and it's value is returned."
  256.     | index count size key |
  257.     size _ self basicSize.
  258.     index _ aKey hash \\ size + 1.
  259.     count _ size.
  260.     [ count > 0 ]
  261.         whileTrue:
  262.         [ key _ self basicAt: index.
  263.               (key isNil or: [ key == aKey ])
  264.             ifTrue: [ ^index ].
  265.           index _ index \\ size + 1.
  266.           count _ count - 1. ].
  267.     ^aBlock value
  268. !
  269.         
  270. findKeyIndex: aKey
  271.     "Finds an association with the given key in the dictionary and returns its
  272.     index.  If the dictionary doesn't contain the object and there is no nil
  273.     element, the dictionary is grown and then the index of where the object
  274.     would go is returned."
  275.     ^self findKeyIndex: aKey
  276.            ifFull: [ self grow.
  277.                 self findKeyIndexNoGrow: aKey
  278.                   ifAbsent: [ ^self error: 'failed to grow a new empty element!!!' ] ]
  279. !
  280.  
  281. grow
  282.     | newDict |
  283.     newDict _ self species new: self basicSize + self growSize.
  284.     self indicesDo: [ :i | newDict at: (self basicAt: i)
  285.                    put: (values basicAt: i) ].
  286.     ^self become: newDict
  287. !
  288.  
  289. growSize
  290.     ^32
  291.  
  292. !!
  293.  
  294.  
  295.